perm filename CH2[206,JMC]1 blob sn#005344 filedate 1971-09-15 generic text, type T, neo UTF8
00100	                             CHAPTER II
00200	
00300	             HOW TO WRITE RECURSIVE FUNCTION DEFINITIONS

00400	
00500	
00600	1. Static and dynamic ways of programming.
00700	
00800		In  order  to  write recursive function definitions, one must
00900	think about programming differently than is  customary  when  writing
01000	programs  in  languages like Fortran or Algol or in machine language.
01100	In these languages, one has in mind the state of the  computation  as
01200	represented  by  the  values of certain variables or locations in the
01300	memory of the machine, and then  one  writes  statements  or  machine
01400	instructions in order to make the state change in an appropriate way.
01500	
01600		When writing LISP recursive functions one thinks differently.
01700	Namely, one thinks about the value of the  function,  asks  for  what
01800	values  of the arguments the value of the function is immediate, and,
01900	given  an  arbitrary  values  of  the  arguments,  for  what  simpler
02000	arguments  must  the  function be known in order to give the value of
02100	the function for  the  given  arguments.  Let  us  take  a  numerical
02200	example;  namely,  suppose  we want to compute the function  n!.  For
02300	what argument is the value of the function immediate.   Clearly,  for
02400	 n = 0  or  n = 1, the value is immediately seen to be  1.  Moreover,
02500	we can get the value for an arbitrary  n  if we know  the  value  for
02600	 n-1.   Also, we see that knowing the value for  n = 1  is redundant,
02700	since it can be obtained from the  n = 0  case by the  same  rule  as
02800	gets  it  for  a  general  n  from the value for  n-1.  All this talk
02900	leads to the simple recursive formula:
03000	
03100		n! ← if n = 0 then 1 else n(n-1)!.
03200	
03300		We may regard this as a static way of looking at programming.
03400	We ask what simpler cases the general case of our function depends on
03500	rather  than  how  we  build up the desired state of the computation.
03600	One often is led to believe that  static = bad  and   dynamic = good,
03700	but  in  this  case,  the static way is often better than the dynamic
03800	way.  LISP offers  both,  but  since  it  is  less  usual,  we  shall
03900	concentrate on the static way for now.
04000	
04100		Compare  the  above  recursive  definition with the following
04200	obvious Algol program for computing  n!:
04300	
04400		integer procedure factorial(n); integer s;
04500	begin
04600		s := 1;
04700	loop:	if n = 0 then go to done;
04800		s := n*s;
04900		n := n-1;
05000		go to loop;
05100	done:	factorial := s;
05200	end;
05300	
05400		The  LISP program is shorter and clearer in this particularly
05500	favorable  case.   Actually,  when  we  discuss  the   mechanism   of
05600	recursion, it will turn out that the LISP program will be inefficient
05700	in using the pushdown mechanism unnecessarily and should be  replaced
05800	by  the  following  somewhat  longer  program that corresponds to the
05900	above Algol program rather precisely:
06000	
06100		n! ← fact(n,s),
06200	
06300	where
06400	
06500		fact(n,s) ← if n = 0 then s else fact(n-1,n*s).
06600	
06700	In  fact,  compilers should produce the same object code from the two
06800	programs.
06900	
07000	
07100	2. Simple list recursion.
07200	
07300		About the simplest form of recursion in LISP occurs when  one
07400	of the arguments is a list, the result is immediate when the argument
07500	is null, and otherwise we need only know the result for the d-part of
07600	that argument.  Consider, for example,  u*v, the concatenation of the
07700	lists  u  and  v.  The result is immediate for  the  case   n u   and
07800	otherwise depends on the result for  d u.  Thus, we have
07900	
08000		u*v ← if n u then v else a u . [d u * v].
08100	
08200	On the other hand, if we had tried to recur on  v  rather than on  u,
08300	we would not have been successful.  The result would be immediate for
08400	 n v, but  u*v  cannot be constructed in any direct way from   u*d v 
08500	without  a  function  that  puts  an  element onto the end of a list.
08600	(From a strictly list point of view, such  a  function  would  be  as
08700	elementary  as  cons  which puts an element onto the front of a list,
08800	but, when we consider the implementation of lists by list structures,
08900	we  see  that  the  function is not so elementary.  This has led some
09000	people to construct systems in which lists are  bi-directional,  but,
09100	in  the  main,  this has turned out to be a bad idea).  Anyway, it is
09200	usually easier to recur on one argument of a function than  to  recur
09300	on the other.
09400	
09500		It  is  often necessary to represent a correspondence between
09600	the elements of a small set of atoms and certain  S-expression  by  a
09700	list structure.  This is conveniently done by means of an association
09800	list which is a list of pairs, each pair consisting of  an  atom  and
09900	the corresponding S-expression. Thus the association list
10000	
10100		((X.(PLUS A B)) (Y.C) (Z.(TIMES U V)),
10200	
10300	which would print as
10400	
10500		((X PLUS A B)) (Y.C) (Z TIMES U V)),
10600	
10750	pairs  X  with  (PLUS A B),  Y  with  C, etc. We need a  function  to
10850	tell  whether  anything  is  associated  with  the  atom   x   in the
10950	association list  a, and, if so, to tell us what. We have
11000	
11100		assoc[x,a] ← if n a then NIL else if x eq aa a then a a
11200			else assoc[x,d a].
11300	
11400	Its value is   NIL   if  nothing  is  associated  with   x   and  the
11500	association pair otherwise.  E.g.  assoc[X,((X.W) (Y.V))] = (X.W).
11600	
11700	
11800		It  commonly happens that a function has no simple recursion,
11900	but there is a simple recursion for a function with one more variable
12000	that  reduces  to the desired function when the extra variable is set
12100	to NIL.  Thus
12200	
12300		reverse[u] ← rev1[x,NIL],
12400	
12500	where
12600	
12700		rev1[u,v] ← if n u then v else rev1[d u,a u . v].
12800	
12900	reverse   has a direct recursive definition as discovered by S. Ness,
13000	but no-one would want to use the following in actual computation  nor
13100	does  it generate much understanding, only appreciation of Mr. Ness's
13200	ingenuity:
13300	
13400		reverse[u] ← if n u ∨ n d u then u else
13500			a reverse[d u] . reverse[a x. reverse[d reverse[d u]]].
13600	
13700	
13800	                              Exercises
13900	
14000		1. Using the function  member[x,u]  defined in Chapter I  and
14100	Which  may also be written  x ε u, write function definitions for the
14200	union  u ∪ v  of lists  u  and  v, the intersection  u ∩ v,  and  the
14300	set  difference   u-v.    What  is  wanted  should  be clear from the
14400	examples:
14500	
14600		(A B C) ∪ (B C D) = (A B C D),
14700	
14800		(A B C) ∩ (B C D) = (B C),
14900	
15000	and
15100	
15200		(A B C) - (B C D) = (A).
15250	
15255	Pay  attention  to betting correct the trivial cases in which some of
15260	the arguments are NIL.  In general, it  is  important  to  understand
15265	clearly the trivial cases of functions.
15300	
15400		2.  Suppose   x   takes  numbers  as  values and  u  takes as
15500	values lists of numbers in ascending order, e.g.  (2 4 7).   Write  a
15600	function   merge[x,u]   whose  value  is obtained from that of  u  by
15700	putting     x     in     u     in    its    proper    place.     Thus
15800	 merge[3,(2 4)] = (2 3 4), and  merge[3,(2 3)] = (2 3 3).
15900	
16000		3.  Write  functions  giving the union, intersection, and set
16100	difference of ordered lists; the result is wanted as an ordered list.
16200	
16300		Note that computing these functions of unordered lists  takes
16400	a  number  of comparisons proportional to the square of the number of
16500	elements of a typical list, while for ordered lists,  the  number  of
16600	comparisons is proportional to the number of elements.
16700	
16800		4.  Using   merge, write a function  sort  that transforms an
16900	unordered list into an ordered list.
17000	
17100		5. Write a function  goodsort  that  sorts  a  list  using  a
17200	number  of  comparisons  proportional  to   n log n, where  n  is the
17300	length of the list to be sorted.
17400	
17500	
17600	3. Simple S-expression recursion.
17700	
17800		In another class of problems, the value of  the  function  is
17900	immediate  for  atomic symbols, and for non atoms depends only on the
18000	values for  the a-part and the d-part of the argument.  Thus   subst 
18100	was defined by
18200	
18300		subst[x,y,z] ← if at z then [if z eq y then x else z]
18400				else subst[x,y,a z].subst[x,y,d z].
18500	
18600		Two other examples are  equal  which gives  the  equality  of
18700	S-expressions  and   flat  which spreads and S-expression into a list
18800	of atoms:  They are defined by
18900	
19000		x=y ← x eq y ∨ [¬at x ∧ ¬at y ∧ a x = a y ∧ d x = d y],
19100	
19200	and
19300	
19400		flat[x] ← flata[x,NIL]
19500	
19600	where
19700	
19800		flata[x,u] ← if at x then x.y else flata[a x,flata[d x,y]].
19900	
20000	
20100	                              EXERCISES
20200	
20300		1. Write a predicate to tell whether a given atom occurs in a
20400	given S-expression, e.g.  occur[B,((A.B).C)] = T.
20500	
20600		2. Write a predicate to tell how  many  times  a  given  atom
20700	occurs in an S-expression.
20800	
20900		3.  Write  a  function to make a list without duplications of
21000	the atoms occurring in an S-expression.
21100	
21200		4. Write a function to make a list of all  atoms  that  occur
21300	more   than   once   in   a  given  S-expression  paired  with  their
21400	multiplicities.
21500	
21600		5. Write a predicate to tell whether an S-expression has more
21700	than one occurrence of a given S-expression as a sub-expression.
21800	
21900	
22000	4. Other structural recursions.
22100	
22200		When lists are used to represent algebraic expressions,
22300	functions of these algebraic expressions often have a
22400	recursive form closely related to the inductive definition of the
22500	expressions.  Suppose, for example, that sums and products are represented
22600	respectively by the forms  (PLUS X Y)  and  (TIMES X Y)  and that the
22700	values of variables are given on an a-list.  We can write a recursive
22800	formula for the value of an expression as follows:
22900	
23000		value[e,a] ← if at e then d assoc[e,a] 
23100				else if a e eq PLUS then value[ad e,a] + value[add e,a]
23200			else if a e eq TIMES then value[ad e,a] * value[add e,a].
23300	
23400	On the other hand, suppose that sums and products are not restricted
23500	to have just two arguments; then we must use auxiliary functions
23600	to define the value of an expression, as follows:
23700	
23800		value[e,a] ← if at e then d assoc[e,a]
23900				else if a e eq PLUS then vplus[d e,a]
24000				else if a e eq TIMES then vtimes[d e,a].
24100	
24200	where
24300	
24400		vplus[u,a] ← if n u then 0 else value[a u,a] + vplus[d u,a],
24500	
24600	and
24700	
24800		vtimes[u,a] ← if n u then 1 else value[a u,a] * vtimes[d u,a].
24900	
25000	In both cases, the recursion form is related to the structure of the
25100	algebraic expressions more closely than to the structure of
25200	S-expressions or lists.
25300	
25400	
25500	5. Tree search.
25600